home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / v3 / bench.lha / bench / nrev.P < prev    next >
Text File  |  1992-08-12  |  980b  |  38 lines

  1. /*  The naive reverse benchmark */
  2.  
  3. nrev([],[]).
  4. nrev([X|Rest],Ans) :- nrev(Rest,L), append(L,[X],Ans).
  5.  
  6. append([],L,L).
  7. append([X|L1],L2,[X|L3]) :-
  8.     append(L1,L2,L3).
  9.  
  10. bench(Count) :- cputime(T0),dodummy(Count),cputime(T1),
  11.     dobench(Count),cputime(T2),
  12.     report(Count,T0,T1,T2).
  13.  
  14. dobench(Count) :- data(List),repeat(Count),nrev(List,_),fail.
  15. dobench(_).
  16.  
  17. dodummy(Count) :- data(List),repeat(Count),dummy(List,_),fail.
  18. dodummy(_).
  19.  
  20. dummy(_,_).
  21.  
  22. data(X) :- data(X,30).
  23. data([],0).
  24. data([a|Y],N) :- N > 0, N1 is N-1, data(Y,N1).
  25. /* data([a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q,r,s,t,u,v,w,x,y,z,aa,bb,cc,dd]). */
  26.  
  27. repeat(N).
  28. repeat(N) :- N > 1, N1 is N-1, repeat(N1).
  29.  
  30. report(Count,T0,T1,T2) :- 
  31.     write('no. of iterations: '), write(Count), nl,
  32.     Time1 is T1 - T0, write('dummy: '), write(Time1),nl,
  33.     Time2 is T2 - T1, write('nrev loop: '), write(Time2),nl,
  34.     Time is Time2-Time1,write('adjusted time: '), write(Time),nl,
  35.     Lips is (496*Count*1000)/Time,
  36.     write('Lips = '),write(Lips), nl.
  37.  
  38.